ConvertUTMtoGeodetic Subroutine

private subroutine ConvertUTMtoGeodetic(x, y, k, centM, lat0, a, e, eb, falseN, falseE, override, lon, lat)

The subroutine converts Universal Transverse Mercator projection (easting and northing) coordinates to geodetic (latitude and longitude) coordinates, according to the current ellipsoid and UTM projection parameters.

Arguments

Type IntentOptional Attributes Name
real(kind=float), intent(in) :: x

easting coordinate [m]

real(kind=float), intent(in) :: y

northing coordinate [m]

real(kind=float), intent(in) :: k

scale factor

real(kind=float), intent(in) :: centM

central meridian [radians]

real(kind=float), intent(in) :: lat0

latitude of origin [radians]

real(kind=float), intent(in) :: a

semimajor axis [m]

real(kind=float), intent(in) :: e

eccentricity

real(kind=float), intent(in) :: eb

second eccentricity

real(kind=float), intent(in) :: falseN

false northing

real(kind=float), intent(in) :: falseE

false easting

real(kind=float), intent(in) :: override

override option

real(kind=float), intent(out) :: lon

geodetic longitude [radians]

real(kind=float), intent(out) :: lat

geodetic latitude [radians]


Variables

Type Visibility Attributes Name Initial
real(kind=float), public, parameter :: MAX_EASTING = 900000.
real(kind=float), public, parameter :: MAX_LAT = 84.5*degToRad
real(kind=float), public, parameter :: MAX_NORTHING = 10000000.
real(kind=float), public, parameter :: MIN_EASTING = 100000.
real(kind=float), public, parameter :: MIN_LAT = -80.5*degToRad
real(kind=float), public, parameter :: MIN_NORTHING = 0.

Source Code

SUBROUTINE ConvertUTMtoGeodetic &
!
!
(x, y, k, centM, lat0, a, e, eb, falseN, falseE, override, lon, lat)

USE StringManipulation, ONLY: &
!Imported routines:
ToString


IMPLICIT NONE

!Arguments with intent(in):
REAL (KIND = float), INTENT (IN) :: x !!easting coordinate [m]
REAL (KIND = float), INTENT (IN) :: y !!northing coordinate [m]
REAL (KIND = float), INTENT (IN) :: k !!scale factor
REAL (KIND = float), INTENT (IN) :: centM !!central meridian [radians]
REAL (KIND = float), INTENT (IN) :: lat0 !!latitude of origin [radians]
REAL (KIND = float), INTENT (IN) :: a !! semimajor axis [m]
REAL (KIND = float), INTENT (IN) :: e !! eccentricity
REAL (KIND = float), INTENT (IN) :: eb !! second eccentricity
REAL (KIND = float), INTENT (IN) :: falseN !!false northing
REAL (KIND = float), INTENT (IN) :: falseE !!false easting
REAL (KIND = float), INTENT (IN) :: override !!override option


!Arguments with intent (out):
REAL (KIND = float), INTENT (OUT) :: lon !!geodetic longitude [radians]
REAL (KIND = float), INTENT (OUT) :: lat !!geodetic latitude [radians]

!Local parameters:
REAL (KIND = float), PARAMETER :: MIN_LAT = -80.5 * degToRad ! -80.5 degrees in radians 
REAL (KIND = float), PARAMETER :: MAX_LAT = 84.5 * degToRad ! 84.5 degrees in radians 
REAL (KIND = float), PARAMETER :: MIN_EASTING = 100000.
REAL (KIND = float), PARAMETER :: MAX_EASTING = 900000.
REAL (KIND = float), PARAMETER :: MIN_NORTHING = 0.
REAL (KIND = float), PARAMETER :: MAX_NORTHING = 10000000.

!------------end of declaration------------------------------------------------

!Check out of range if override is off
IF ( override == 0. ) THEN
    IF ( x < MIN_EASTING .OR. x > MAX_EASTING ) THEN
      CALL Catch ('error', 'GeoLib',   &
			      'Converting UTM to Geodetic: &
			       easting out of range' ,  &
			       code = consistencyError, argument = ToString(x) )
    END IF
    IF ( y < MIN_NORTHING .OR. y > MAX_NORTHING ) THEN
      CALL Catch ('error', 'GeoLib',   &
			      'Converting UTM to Geodetic: &
			       northing out of range' ,  &
			       code = consistencyError, argument = ToString(y) )
    END IF
END IF

CALL ConvertTransverseMercatorToGeodetic (x, y, k, centM, lat0, a, e, eb, &
                                          falseN, falseE, lon, lat)
                                          
IF ( lat < MIN_LAT .OR. lat > MAX_LAT ) THEN
  CALL Catch ('error', 'GeoLib',   &
			 'Converting UTM to Geodetic: &
			 latitude out of range ' ,  &
			 code = consistencyError, &
			 argument = ToString(lat*radToDeg)//' deg' )
END IF                                          

END SUBROUTINE ConvertUTMtoGeodetic